InitRasterExport Subroutine

public subroutine InitRasterExport(fileini, temp, precipitation, rh, radiation, netradiation, windspeed, swe, sm, runoff, infiltration, percolation, et, pet)

Initialization of raster export

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fileini
type(grid_real), intent(in) :: temp

air temperarure (°C)

type(grid_real), intent(in) :: precipitation

precipitation rate (m/s)

type(grid_real), intent(in) :: rh

air relative humidity (0-100)

type(grid_real), intent(in) :: radiation

solar radiation (w/m2)

type(grid_real), intent(in) :: netradiation

net radiation (w/m2)

type(grid_real), intent(in) :: windspeed

wind speed (m/s)

type(grid_real), intent(in) :: swe

snow water equivalent (m)

type(grid_real), intent(in) :: sm

soil mositure (-)

type(grid_real), intent(in) :: runoff

runoff (m/s)

type(grid_real), intent(in) :: infiltration

infiltration (m/s)

type(grid_real), intent(in) :: percolation

deep percolation (m/s)

type(grid_real), intent(in) :: et

actual evapotranspiration (m/s)

type(grid_real), intent(in) :: pet

potential evapotranspiration (m/s)


Variables

Type Visibility Attributes Name Initial
type(IniList), public :: iniDB
character(len=300), public :: string

Source Code

SUBROUTINE InitRasterExport   & 
!
 (fileini, temp, precipitation, &
  rh, radiation, netradiation, windspeed, &
  swe, sm, runoff, infiltration, percolation, et, pet)  

IMPLICIT NONE

!arguments with intent in:
CHARACTER (LEN = *), INTENT(IN)    :: fileini   
TYPE (grid_real), INTENT(IN) :: temp !!air temperarure (°C)
TYPE (grid_real), INTENT(IN) :: precipitation !!precipitation rate (m/s)
TYPE (grid_real), INTENT(IN) :: rh !!air relative humidity (0-100)
TYPE (grid_real), INTENT(IN) :: radiation !!solar radiation (w/m2)
TYPE (grid_real), INTENT(IN) :: netradiation !!net radiation (w/m2)
TYPE (grid_real), INTENT(IN) :: windspeed !!wind speed (m/s)
TYPE (grid_real), INTENT(IN) :: swe !!snow water equivalent (m)
TYPE (grid_real), INTENT(IN) :: sm !!soil mositure (-)
TYPE (grid_real), INTENT(IN) :: runoff !!runoff (m/s)
TYPE (grid_real), INTENT(IN) :: infiltration !!infiltration (m/s)
TYPE (grid_real), INTENT(IN) :: percolation !!deep percolation (m/s)
TYPE (grid_real), INTENT(IN) :: et !!actual evapotranspiration (m/s)
TYPE (grid_real), INTENT(IN) :: pet !!potential evapotranspiration (m/s)

 

!local declarations
TYPE (IniList)          :: iniDB
CHARACTER (LEN = 300)  :: string
!-------------------------------end of declaration-----------------------------

!initialize counter
countSteps = 0

!  open and read configuration file
CALL IniOpen (fileini, iniDB)

! configure time to export data
IF (KeyIsPresent ('time', iniDB) ) THEN
    string =  IniReadString ('time', iniDB)
    CALL CronParseString (string, cron) 
ELSE
    CALL Catch ('error', 'RasterExport', &
            'missing time ' )
END IF

! set template for exported raster
IF (SectionIsPresent ('map-template', iniDB) ) THEN
    useTemplate = .TRUE.
    CALL GridByIni (iniDB, rasterTemplate, section = 'map-template')
    gridTemp % grid_mapping = rasterTemplate % grid_mapping 
    CALL NewGrid ( gridTemp2, rasterTemplate )
ELSE
    useTemplate = .FALSE.
    CALL NewGrid (rasterTemplate, mask) 
END IF

! set out folder
IF (KeyIsPresent ('folder', iniDB) ) THEN
    pathout =  IniReadString ('folder', iniDB)
ELSE
    CALL Catch ('error', 'RasterExport', &
            'missing folder for output ' )
END IF

! search for active variable for output
CALL Catch ('info', 'RasterExport', 'checking for active variables ')

countVar = 0

!precipitation
IF ( IniReadInt ('precipitation', iniDB, section = 'meteo') == 1) THEN
   IF ( .NOT. ALLOCATED (temp % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'air-temperature not allocated, &
                                        forced to not export raster ')
       varOut (1) = .FALSE.
   ELSE
       varOut (1) = .TRUE.
       CALL NewGrid (rasterPrecipitation, rasterTemplate)
       
   END IF
ELSE
   varOut (1) = .FALSE.
END IF

!air-temperature
IF ( IniReadInt ('temperature', iniDB, section = 'meteo') == 1) THEN
   IF ( .NOT. ALLOCATED (precipitation % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'precipitation not allocated, &
                                        forced to not export raster ')
       varOut (2) = .FALSE.
   ELSE
       varOut (2) = .TRUE.
       CALL NewGrid (rasterTemperature, rasterTemplate)
       
   END IF
ELSE
   varOut (2) = .FALSE.
END IF

!relative-humidity
IF ( IniReadInt ('relative-humidity', iniDB, section = 'meteo') == 1) THEN
   IF ( .NOT. ALLOCATED (rh % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'relative humidity not allocated, &
                                        forced to not export raster ')
       varOut (3) = .FALSE.
   ELSE
       varOut (3) = .TRUE.
       CALL NewGrid (rasterRH, rasterTemplate)
       
   END IF
ELSE
   varOut (3) = .FALSE.
END IF


!solar-radiation
IF ( IniReadInt ('solar-radiation', iniDB, section = 'meteo') == 1) THEN
   IF ( .NOT. ALLOCATED (radiation % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'solar radiation not allocated, &
                                        forced to not export raster ')
       varOut (4) = .FALSE.
   ELSE
       varOut (4) = .TRUE.
       CALL NewGrid (rasterRad, rasterTemplate)
       
   END IF
ELSE
   varOut (4) = .FALSE.
END IF


!net-radiation
IF ( IniReadInt ('net-radiation', iniDB, section = 'meteo') == 1) THEN
   IF ( .NOT. ALLOCATED (netradiation % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'net radiation not allocated, &
                                        forced to not export raster ')
       varOut (5) = .FALSE.
   ELSE
       varOut (5) = .TRUE.
       CALL NewGrid (rasterNetRad, rasterTemplate)
       
   END IF
ELSE
   varOut (5) = .FALSE.
END IF


!wind-speed
IF ( IniReadInt ('wind-speed', iniDB, section = 'meteo') == 1) THEN
   IF ( .NOT. ALLOCATED (windspeed % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'wind speed not allocated, &
                                        forced to not export raster ')
       varOut (6) = .FALSE.
   ELSE
       varOut (6) = .TRUE.
       CALL NewGrid (rasterWS, rasterTemplate)
       
   END IF
ELSE
   varOut (6) = .FALSE.
END IF

!snow-water-equivalent
IF ( IniReadInt ('snow-water-equivalent', iniDB, section = 'snow') == 1) THEN
   IF ( .NOT. ALLOCATED (swe % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'snow water equivalent not allocated, &
                                        forced to not export raster ')
       varOut (7) = .FALSE.
   ELSE
       varOut (7) = .TRUE.
       CALL NewGrid (rasterSWE, rasterTemplate)
       
   END IF
ELSE
   varOut (7) = .FALSE.
END IF

!soil-moisture
IF ( IniReadInt ('soil-moisture', iniDB, section = 'soil-balance') == 1) THEN
   IF ( .NOT. ALLOCATED (sm % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'soil moisture not allocated, &
                                        forced to not export raster ')
       varOut (8) = .FALSE.
   ELSE
       varOut (8) = .TRUE.
       CALL NewGrid (rasterSM, rasterTemplate)
       
   END IF
ELSE
   varOut (8) = .FALSE.
END IF

!runoff
IF ( IniReadInt ('runoff', iniDB, section = 'soil-balance') == 1) THEN
   IF ( .NOT. ALLOCATED (runoff % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'runoff not allocated, &
                                        forced to not export raster ')
       varOut (9) = .FALSE.
   ELSE
       varOut (9) = .TRUE.
       CALL NewGrid (rasterRunoff, rasterTemplate)
       
   END IF
ELSE
   varOut (9) = .FALSE.
END IF

!infiltration
IF ( IniReadInt ('infiltration', iniDB, section = 'soil-balance') == 1) THEN
   IF ( .NOT. ALLOCATED (infiltration % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'infiltration not allocated, &
                                        forced to not export raster ')
       varOut (10) = .FALSE.
   ELSE
       varOut (10) = .TRUE.
       CALL NewGrid (rasterInfiltration, rasterTemplate)
       
   END IF
ELSE
   varOut (10) = .FALSE.
END IF

!percolation
IF ( IniReadInt ('percolation', iniDB, section = 'soil-balance') == 1) THEN
   IF ( .NOT. ALLOCATED (percolation % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'percolation not allocated, &
                                        forced to not export raster ')
       varOut (11) = .FALSE.
   ELSE
       varOut (11) = .TRUE.
       CALL NewGrid (rasterPercolation, rasterTemplate)
       
   END IF
ELSE
   varOut (11) = .FALSE.
END IF

!actual-ET
IF ( IniReadInt ('actual-ET', iniDB, section = 'soil-balance') == 1) THEN
   IF ( .NOT. ALLOCATED (et % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'ET not allocated, &
                                        forced to not export raster ')
       varOut (12) = .FALSE.
   ELSE
       varOut (12) = .TRUE.
       CALL NewGrid (rasterET, rasterTemplate)
       
   END IF
ELSE
   varOut (12) = .FALSE.
END IF

!potential-ET
IF ( IniReadInt ('potential-ET', iniDB, section = 'soil-balance') == 1) THEN
   IF ( .NOT. ALLOCATED (pet % mat) ) THEN
       CALL Catch ('warning', 'RasterExport', 'PET not allocated, &
                                        forced to not export raster ')
       varOut (13) = .FALSE.
   ELSE
       varOut (13) = .TRUE.
       CALL NewGrid (rasterPET, rasterTemplate)
       
   END IF
ELSE
   varOut (13) = .FALSE.
END IF


CALL IniClose (iniDB) 


!Initialize times
!timeNewTemp = time

RETURN
END SUBROUTINE InitRasterExport